home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Libris Britannia 4
/
science library(b).zip
/
science library(b)
/
UTILITIE
/
CPU_MEMO
/
3468.ZIP
/
POPUP.ZIP
/
POPUP.ASM
< prev
next >
Wrap
Assembly Source File
|
1988-06-30
|
14KB
|
388 lines
;-----------------------------------------------------------------------------
; POPUP.ASM : A popup utility for linking with Microsoft 'C'
;-----------------------------------------------------------------------------
; Last Updated : 04/01/80
;-----------------------------------------------------------------------------
; Author : M.R.Watson. Copyright (C) M.R.Watson, 1987, 1988
;-----------------------------------------------------------------------------
; Synopsis
; ========
; This implements a function, "popup", which can be called by any small model
; Microsoft 'C' program. Calling is as follows :
; popup( int ScanCode, int ShiftCode )
; where ScanCode is the activating key's scan code, and ShiftCode is the
; combination of shift codes, as defined in documentation for interrupt 16H.
; This allows you to choose, for example, CTRL-ALT-ESC as the activating key.
; (Scan code = 1, shift code = 0CH)
; Once popup() has been called, as far as the program is concerned it returns
; after an unspecified period of time. What actually happens is that the
; program initialises various interrupt vectors, and then terminates and
; stays resident. When the activating key-sequence is pressed, the program
; interrupts, and control returns to the part of the program which just called
; popup() as if that function (popup()) had just returned.
; Then the program can proceed with the popup code as it sees fit.
; Note that the only DOS services which may be used are int 21H, function
; codes 0DH and above. This effectively precludes the use of DOS console IO.
; You must therefore use BIOS to do this, or write directly to video memory.
; In order to maintain compatiblity with Sidekick, et al, it is sensible to
; continuously issue interrupt 28H (background process), which Sidekick
; uses in the same way as this program.
;
; Note that this program uses two undocumented features of MS-DOS :
;
; (1) Interrupt 28H. This is called continuously by int 21H func 0AH
; (buffered input), and hence by anything which calls func 0AH.
; When this interrupt is recieved, any DOS function HIGHER that 0CH
; may be freely called.
; (2) Int 21H, func 34H. Returns ES:BX pointing to a byte which is the DOS
; busy flag. When this flag is TRUE (non-zero), DOS is busy and shouldn't
; be interrupted. When it is false (0), any DOS function may be called.
; A combination of these two features is used to enable the popup() function
; to popup without conflict at the earliest possible moment.
;
; NOTE: It is a good idea to EXEMOD the resulting program, and change the
; maximum paragraph allocation in order to make it take up less memory.
;-----------------------------------------------------------------------------
; EXAMPLE :
;
; FOREVER
; {
; popup( ScanCode, ShiftStatus );
; HandlePopup();
; }
;-----------------------------------------------------------------------------
; Assembly notes:
; ---------------
; This is compiled with MASM 5.0. To use an earlier version, you will have to
; define the code and data segments in the usual way. Also, one line
; (the .MODEL directive) must be removed from the file CLINK.INC
; (The CLINK.INC header may also be useful in other assembly programs.)
;-----------------------------------------------------------------------------
PUBLIC _popup
include CLINK.INC
.DATA
EXTRN __psp:WORD
.CODE
OldKeyboard LABEL DWORD ; Old keyboard interrupt address
oldint9h dw 2 dup (?)
OldTimer LABEL DWORD ; Old timer interrupt address
oldint1ch dw 2 dup (?)
OldDisk LABEL DWORD ; Old disk service interrupt address
oldint13h dw 2 dup (?)
OldBackground LABEL DWORD ; Old background process int address
oldint28h dw 2 dup (?)
ScanCode db 0 ; Scan code of activating key.
ShiftCode db 0 ; Shift status required for activation.
PopupActive db 0 ; Set to 0FFH when popup is active.
PopupWanted db 0 ; Set to 0FFH when popup wanted.
DiskActive db 0 ; Set to 0FFH when disk is active (Int 13H)
installed db 0 ; Set to 0FFH after Popup is installed
DosSegment dw ?
BusyFlag dw ?
PopAX dw ?
PopBX dw ?
PopCX dw ?
PopDX dw ?
PopSI dw ?
PopDI dw ?
PopSS dw ?
PopSP dw ?
PopBP dw ?
PopDS dw ?
PopES dw ?
DosAX dw ?
DosBX dw ?
DosCX dw ?
DosDX dw ?
DosSI dw ?
DosDI dw ?
DosSS dw ?
DosSP dw ?
DosBP dw ?
DosDS dw ?
DosES dw ?
;-----------------------------------------------------------------------------
; Keyboard Interrupt Handler (Interrupt 09H)
;-----------------------------------------------------------------------------
keyboard PROC NEAR
sti ; Enable interrupts
push ax
in al, 60H ; Get keyboard scan code
cmp al, ScanCode ; Matches ScanCode ?
jne CallKeyboard ; No - Call original routine
mov ah, 2 ; BIOS func : Check shift status
int 16H ; Call it...
and al, 15 ; Ignore numlock etc
cmp al, ShiftCode ; Matches ShiftCode ?
jne CallKeyboard ; No - Call original routine
call ResetKeyboard ; Actuator, so remove from keyboard.
pop ax
cmp PopupActive, 0FFH ; Popup already active?
je KeyDone ; No more to do if so.
mov PopupWanted, 0FFH ; Else set request flag.
KeyDone:
iret
CallKeyboard:
pop ax
jmp OldKeyboard ; Call original int 9 handler, which
; will do it's own iret.
keyboard ENDP
;-----------------------------------------------------------------------------
; Timer Interrupt handler (Interrupt 1CH)
;-----------------------------------------------------------------------------
timer PROC NEAR
pushf
call OldTimer
cmp PopupWanted, 0 ; Is a popup requested ?
je TimerExit
push es
push di
mov es, DosSegment ; Get seg:off of busy flag
mov di, BusyFlag
cmp BYTE PTR es:[di], 0 ; Is DOS busy?
pop di
pop es
jne TimerExit ; If so, don't pop up
cmp DiskActive, 0 ; Is a disk service active?
jne TimerExit ; If so, don't pop up
push ax
mov al, 20H
out 20H, al ; Issue EOI to 8259 PIC
pop ax
mov PopupWanted, 0
call poppit ; Call the actual popup routine
TimerExit:
iret
timer ENDP
;-----------------------------------------------------------------------------
; Disk Service Interrupt Handler (Interrupt 13H)
;-----------------------------------------------------------------------------
DiskService PROC NEAR
inc DiskActive
pushf
call OldDisk
dec DiskActive
iret
DiskService ENDP
;-----------------------------------------------------------------------------
; Background Process Interrupt Handler (Interrupt 28H)
;-----------------------------------------------------------------------------
background PROC NEAR
pushf
call OldBackground
cmp PopupWanted, 0 ; Want to popup ?
je BackgroundExit ; No - Exit
mov PopupWanted, 0 ; Reset popup wanted flag
call poppit ; Call the actual popup routine
BackgroundExit:
iret
background ENDP
;-----------------------------------------------------------------------------
; ResetKeyboard : Does just that.
;-----------------------------------------------------------------------------
ResetKeyboard PROC NEAR
in al, 61H ; Get current control value
mov ah, al
or al, 80H ; Set high bit
out 61H, al ; Send to control port
mov al, ah ; Recover original value
out 61h, al ; And send it
cli
mov al, 20H
out 20H, al ; Send EOI to 8259 PIC
sti
ret
ResetKeyboard ENDP
;-----------------------------------------------------------------------------
; poppit : This is the routine called when a popup has been requested.
;-----------------------------------------------------------------------------
poppit PROC NEAR
mov PopupActive, 0FFH
sti
mov WORD PTR DosAX, ax ; Save Dosup register block
mov WORD PTR DosBX, bx
mov WORD PTR DosCX, cx
mov WORD PTR DosDX, dx
mov WORD PTR DosSI, si
mov WORD PTR DosDI, di
mov WORD PTR DosSP, sp
mov WORD PTR DosBP, bp
mov WORD PTR DosSS, ss
mov WORD PTR DosES, es
mov WORD PTR DosDS, ds
mov ax, WORD PTR PopAX
mov bx, WORD PTR PopBX
mov cx, WORD PTR PopCX
mov dx, WORD PTR PopDX
mov si, WORD PTR PopSI
mov di, WORD PTR PopDI
mov bp, WORD PTR PopBP
cli
mov sp, WORD PTR PopSP
mov ss, WORD PTR PopSS
sti
mov es, WORD PTR PopES
mov ds, WORD PTR PopDS
ret
poppit ENDP
;-----------------------------------------------------------------------------
; Entry point for calls to Popup() : Initialise if necessary.
;-----------------------------------------------------------------------------
; Example usage :
;
; FOREVER
; {
; popup(ScanCode,ShiftCode);
; /* Code to handle popup */
; }
;-----------------------------------------------------------------------------
_popup PROC NEAR
mov PopupActive, 0FFH ; Just in case of timer ints.
mov WORD PTR PopAX, ax ; Save Popup register block
mov WORD PTR PopBX, bx
mov WORD PTR PopCX, cx
mov WORD PTR PopDX, dx
mov WORD PTR PopSI, si
mov WORD PTR PopDI, di
mov WORD PTR PopSP, sp
mov WORD PTR PopBP, bp
mov WORD PTR PopSS, ss
mov WORD PTR PopES, es
mov WORD PTR PopDS, ds
cmp installed, 0 ; Already installed ?
je install ; No - So go to it
mov ax, WORD PTR DosAX
mov bx, WORD PTR DosBX
mov cx, WORD PTR DosCX
mov dx, WORD PTR DosDX
mov si, WORD PTR DosSI
mov di, WORD PTR DosDI
mov bp, WORD PTR DosBP
cli
mov sp, WORD PTR DosSP
mov ss, WORD PTR DosSS
sti
mov es, WORD PTR DosES
mov ds, WORD PTR DosDS
mov PopupActive, 0
ret
install:
DEFARGS scan, WORD, shift, WORD
push ds
push cs
pop ds
mov installed, 0FFH
MOVARG ax, scan ; Save activator key codes
mov ScanCode, al
MOVARG ax, shift
mov ShiftCode, al
mov ah, 34H ; Undocumented DOS function! Get busy flag.
int 21H ; Returns es:[BX] = Busy flag
mov DosSegment, es ; So save for later usage
mov BusyFlag, bx
mov ah, 35h ; DOS func: Get interrupt vector
mov al, 09h ; Get vector 09H
int 21h
mov oldint9h, bx ; And save here
mov oldint9h[2], es
mov ah, 25H ; DOS func: Set interrupt vector
lea dx, keyboard
int 21H
mov ah, 35H ; Save & set timer interrupt vector
mov al, 1cH
int 21h
mov oldint1ch, bx
mov oldint1ch[2], es
mov ah, 25h
lea dx, timer
int 21h
mov ah, 35h ; Save & set disk service interrupt vector
mov al, 13h
int 21h
mov oldint13h, bx
mov oldint13h[2], es
mov ah, 25h
lea dx, DiskService
int 21h
mov ah, 35h ; Save & set background process int. vector
mov al, 28h
int 21h
mov oldint28h, bx
mov oldint28h[2], es
mov ah, 25h
lea dx, background
int 21h
pop ds
mov ah,31h ; load keep process code
mov al,0 ; load normal termination
mov es, __psp
mov dx, es:[2]
mov bx, cs
sub dx, bx
add dx, 10H
inc dx
mov PopupActive, 0
pop bp ; Was pushed by DEFARGS macro
int 21h ; terminate and stay resident
_popup ENDP
END